Sync Subroutine

public subroutine Sync(first, last, iniDB, sec, subSec)

synchronize the window in which searching for the key

Arguments

Type IntentOptional Attributes Name
integer(kind=long), intent(out) :: first
integer(kind=long), intent(out) :: last
type(IniList), intent(in) :: iniDB
character(len=*), intent(in), optional :: sec
character(len=*), intent(in), optional :: subSec

Variables

Type Visibility Attributes Name Initial
integer(kind=long), public :: i
integer(kind=long), public :: j

Source Code

SUBROUTINE Sync &
!
(first,last,iniDB,sec,subSec)

IMPLICIT NONE

! subroutine arguments 
! Scalar arguments with intent(in):
CHARACTER (LEN = *), OPTIONAL, INTENT(IN) :: sec
CHARACTER (LEN = *), OPTIONAL, INTENT(IN) :: subSec
TYPE (IniList), INTENT (IN) :: iniDB

! Scalar arguments with intent(out): 
INTEGER (KIND = long), INTENT (OUT) :: first
INTEGER (KIND = long), INTENT (OUT) :: last

! Local Scalars:
INTEGER (KIND = long) :: i ! loop index 
INTEGER (KIND = long) :: j ! loop index 

!------------end of declaration------------------------------------------------


! if not present section and subsection key must to be serached in the root
IF ( .NOT.PRESENT (sec) .AND. .NOT.PRESENT (subSec) ) THEN
	first = 1
	IF ( iniDB % sectionBegin(1) == 0) THEN !there are not sections in ini file
		last = iniDB % numKeys
	ELSE  !root terminates one element before first section begin
		last = iniDB % sectionBegin(1) - 1  
	ENDIF	
ENDIF

! if present section limit window to that section
IF ( PRESENT (sec) .AND. .NOT.PRESENT (subSec) ) THEN

	DO i = 1, iniDB % nOfSections
		IF (iniDB % sectionName (i) == sec) THEN
			EXIT !found section
		ENDIF 
	ENDDO

	first = iniDB % sectionBegin (i)
	last  = iniDB % sectionEnd (i)
ENDIF

! if present subsection limit window to that subsection
IF ( PRESENT (sec) .AND. PRESENT (subSec) ) THEN

	DO i = 1, iniDB % nOfSections
		IF (iniDB % sectionName (i) == sec) THEN
			EXIT !found section
		ENDIF 
	ENDDO
	
	!search for subsection in the section
	DO j = 1, iniDB % nOfSubSections

		IF (iniDB % subSectionName (j) == subSec) THEN
			IF (iniDB % subSectionBegin (j) >= iniDB % sectionBegin (i) .AND. &
				iniDB % subSectionEnd (j) <= iniDB % sectionEnd (i) ) THEN
				EXIT !found subsection
			ELSE
				CYCLE
			ENDIF				
		ENDIF 

	ENDDO

	first = iniDB % subSectionBegin (j)
	last  = iniDB % subSectionEnd (j)
	
ENDIF

RETURN
END SUBROUTINE Sync